home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Libris Britannia 4
/
science library(b).zip
/
science library(b)
/
DDJMAG
/
DDJ9207.ZIP
/
ACOMP.ZIP
/
UC.ASM
< prev
next >
Wrap
Assembly Source File
|
1992-04-13
|
6KB
|
228 lines
;; UC.ASM -> Uncompress ACOMP compressed audio data.
;; Written by John W. Ratcliff, 1991.
;; Uses Turbo Assembler IDEAL mode.
IDEAL ; Enter Turbo Assembler IDEAL mode.
JUMPS ; Allow automatic jump sizing.
INCLUDE "prologue.mac" ; Include common useful assembly macros.
SMALL_MODEL equ 0 ;: true only if trying to generate near calls
SETUPSEGMENT ; Setup _TEXT segment.
Macro CPROC name
public _&name
IF SMALL_MODEL
Proc _&name near
ELSE
Proc _&name far
ENDIF
endm
SQLCH equ 64 ; Squelch byte flag
RESYNC equ 128 ; Resync byte flag.
DELTAMOD equ 00110000b ; Bit mask for delta mod bits.
ONEBIT equ 00010000b ; Bit pattern for one bit delta mod.
TWOBIT equ 00100000b ; Bit pattern for two bit delta mod.
FOURBIT equ 00110000b ; Bit pattern for two bit delta mod.
base dw ? ; Base address inside translate table.
TRANS db -8,-7,-6,-5,-4,-3,-2,-1,1,2,3,4,5,6,7,8
db -16,-14,-12,-10,-8,-6,-4,-2,2,4,6,8,10,12,14,16
db -24,-21,-18,-15,-12,-9,-6,-3,3,6,9,12,15,18,21,24
db -32,-28,-24,-20,-16,-12,-8,-4,4,8,12,16,20,24,28,32
db -40,-35,-30,-25,-20,-15,-10,-5,5,10,15,20,25,30,35,40
db -48,-42,-36,-30,-24,-18,-12,-6,6,12,18,24,30,36,42,48
db -56,-49,-42,-35,-28,-21,-14,-7,7,14,21,28,35,42,49,56
db -64,-56,-48,-40,-32,-24,-16,-8,8,16,24,32,40,48,56,64
db -72,-63,-54,-45,-36,-27,-18,-9,9,18,27,36,45,54,63,72
db -80,-70,-60,-50,-40,-30,-20,-10,10,20,30,40,50,60,70,80
db -88,-77,-66,-55,-44,-33,-22,-11,11,22,33,44,55,66,77,88
db -96,-84,-72,-60,-48,-36,-24,-12,12,24,36,48,60,72,84,96
db -104,-91,-78,-65,-52,-39,-26,-13,13,26,39,52,65,78,91,104
db -112,-98,-84,-70,-56,-42,-28,-14,14,28,42,56,70,84,98,112
db -120,-105,-90,-75,-60,-45,-30,-15,15,30,45,60,75,90,105,120
db -128,-112,-96,-80,-64,-48,-32,-16,16,32,48,64,80,96,112,127
CPROC GetFreq ; Report playback frequency for an ACOMP file.
ARG SOURCE:DWORD
PENTER 0
push es
les bx,[SOURCE]
mov ax,[es:bx+2]
pop es
PLEAVE
ret
endp
;; DX contains PREVIOUS.
;; AH contains bit mask being rotated out.
;; BX up/down 1 bit value.
Macro Delta1
LOCAL @@UP,@@STORE
shl ah,1 ; Rotate bit mask out.
jc @@UP
sub dx,bx
jns @@STORE
xor dx,dx ; Zero it out.
jmp short @@STORE
@@UP: add dx,bx
or dh,dh
jz @@STORE
mov dx,255
@@STORE:mov al,dl ; Store result.
stosb
endm
;; BX-> base address of translate table.
;; DX-> previous.
;; AL-> index.
Macro DeModulate
LOCAL @@HIGH,@@OK
xlat [cs:bx] ; Translate into lookup table.
cbw ; Make it a signed word.
add dx,ax ; Do word sized add, into previous.
jns @@HIGH
xor dx,dx ; Underflowed.
@@HIGH: or dh,dh ; Did it overflow?
jz @@OK
mov dx,255 ; Maxed out.
@@OK: mov al,dl
stosb
endm
;;unsigned int far UnCompressAudio(unsigned char far *source,unsigned char far *dest);
;; UnCompressAudio will decompress data which was compressed using ACOMP
;; into the destination address provided. UnCompressAudio returns the
;; total size, in bytes, of the uncompressed audio data.
CPROC UnCompressAudio
ARG SHAN:DWORD,DHAN:DWORD
LOCAL SLEN:WORD,FREQ:WORD,FRAME:WORD,BITS:WORD = LocalSpace
PENTER LocalSpace
PushCREGS
lds si,[SHAN] ; Get source segment
les di,[DHAN] ; Get destination segment
lodsw ; Get length.
mov [SLEN],ax ; Save length.
mov cx,ax ; Into CX
lodsw ; Frequency.
mov [FREQ],ax ; Save frequency
lodsb ; Get frame size.
xor ah,ah ; Zero high byte
mov [FRAME],ax ; Save it.
lodsb ; Get squelch, and skip it.
lodsw ; Get maximum error, and skip it.
lodsb ; Get initial previous data point.
stosb ; Store it.
xor ah,ah ; zero high byte.
mov dx,ax ; Save into previous word.
dec cx ; Decrement total by one.
jz @@DONE ; Exit
mov ah,al ; AH, always the previous.
@@DCMP: lodsb ; Get sample.
test al,RESYNC ; Resync byte?
jz @@NOTR ; no, skip.
shl al,1 ; Times two.
mov dl,al ; Into previous.
xor dh,dh ; Zero high word.
stosb ; Store it.
loop @@DCMP ; Next one.
jmp @@DONE
@@NOTR: test al,SQLCH ; Squelch byte?
jz @@FRAM ; no, then it is a frame.
and al,00111111b ; Leave just the count.
push cx ; Save current countdown counter.
mov cl,al ; get repeat count
xor ch,ch ; zero high byte of CX
mov bx,cx ; Repeat count in DX
mov al,dl ; Repeat of previous.
rep stosb ; Repeat it.
pop cx ; Get back remaining count.
sub cx,bx ; Less.
jnz @@DCMP ; Keep going.
jmp @@DONE
@@FRAM:
mov bx,ax ; command byte into BX
and bx,0Fh ; Multiplier being used.
ShiftL bx,4 ; Times 16.
add bx,offset TRANS ; Plus address of translate table.
and al,DELTAMOD ; Leave just delta mod.
push cx
mov cx,[FRAME] ; Get frame size.
cmp al,ONEBIT ; In one bit delta mod?
jne @@NEXT1 ; no, try other.
ShiftR cx,3 ; /8
mov bl,[cs:bx+8] ; Get up amount
xor bh,bh ; Zero high byte.
@@GO: lodsb
xchg al,ah ; Place prev in AL, Bit mask in AH
Delta1
Delta1
Delta1
Delta1
Delta1
Delta1
Delta1
Delta1
mov ah,al
loop @@GO
jmp @@RENTER
@@NEXT1:cmp al,TWOBIT ; In two bit delta mod mode?
jne @@NEXT2
add bx,6 ; Point at +- 2 bit's in table.
shr cx,1
shr cx,1 ; 4 samples per byte.
@@GOGO: lodsb
ShiftR al,6
DeModulate
mov al,[ds:si-1]
ShiftR al,4
and al,3
DeModulate
mov al,[ds:si-1]
ShiftR al,2
and al,3
DeModulate
mov al,[ds:si-1]
and al,3
DeModulate
loop @@GOGO
jmp short @@RENTER
@@NEXT2:shr cx,1 ; Two samples per byte.
@@GO2: lodsb ; Get sample.
ShiftR al,4
DeModulate
mov al,[ds:si-1]
and al,0Fh
DeModulate
loop @@GO2
@@RENTER:
pop cx
sub cx,[FRAME]
jnz @@DCMP ; Continue decompress
@@DONE:
mov ax,[SLEN] ; Uncompressed length.
PopCREGS
PLEAVE
ret
endp
ENDS
END